GetDtGrid Function

public function GetDtGrid(filename, checkRegular) result(dt)

Arguments

Type IntentOptional Attributes Name
character(len=*), intent(in) :: filename
logical, intent(in), optional :: checkRegular

Return Value integer(kind=long)


Variables

Type Visibility Attributes Name Initial
character(len=80), public :: attribute
type(DateTime), public :: date1
type(DateTime), public :: date2
integer, public, DIMENSION(NF90_MAX_VAR_DIMS) :: dimIDs
integer(kind=short), public :: i
integer(kind=short), public :: idTime

Id of the variable containing information on time coordinate

integer(kind=short), public :: length

length of time dimension

integer(kind=short), public :: nAtts

number of global attributes

integer(kind=short), public :: nDims

number of dimensions

integer(kind=short), public :: nVars

number of variables

integer(kind=short), public :: ncId

NetCdf Id for the file

integer(kind=short), public :: ncStatus

error code returned by NetCDF routines

type(DateTime), public :: ref_time
integer, public :: slice(1)
integer, public :: slice2(2)
character(len=19), public :: str
character(len=19), public :: str1
character(len=19), public :: str2
integer, public :: time1
integer, public :: time2
integer(kind=short), public :: timeDimId

id of time dimension

integer, public :: timeSpan
character(len=25), public :: timeString
character(len=7), public :: time_unit
character(len=100), public :: variableName

Source Code

FUNCTION GetDtGrid &
!
(filename, checkRegular) &
!
RESULT (dt)

USE Units, ONLY: &
! Imported parameters:
minute, hour, day, month

USE StringManipulation, ONLY: &
! imported routines:
ToString

IMPLICIT NONE

!Arguments with intent(in):
CHARACTER (LEN = *), INTENT(IN) :: filename
LOGICAL, OPTIONAL, INTENT(IN)   :: checkRegular

!Local declarations:
INTEGER (KIND = long)  :: dt
INTEGER (KIND = short) :: ncStatus !!error code returned by NetCDF routines
INTEGER (KIND = short) :: ncId  !!NetCdf Id for the file
INTEGER (KIND = short) :: nDims !!number of dimensions
INTEGER (KIND = short) :: nVars !!number of variables
INTEGER (KIND = short) :: nAtts !!number of global attributes
INTEGER (KIND = short) :: timeDimId !!id of time dimension
INTEGER (KIND = short) :: length !!length of time dimension
INTEGER (KIND = short) :: idTime !!Id of the variable containing 
                                 !!information on time coordinate         
CHARACTER (LEN = 80)   :: attribute
CHARACTER (LEN = 25)   :: timeString
CHARACTER (LEN = 100)  :: variableName
TYPE(DateTime)         :: ref_time
TYPE(DateTime)         :: date1, date2
CHARACTER (LEN = 7)    :: time_unit
INTEGER                :: slice (1)
INTEGER                :: slice2 (2)
INTEGER                :: time1, time2
INTEGER                :: timeSpan
INTEGER (KIND = short) :: i
INTEGER, DIMENSION(NF90_MAX_VAR_DIMS) :: dimIDs
CHARACTER (LEN = 19)   :: str, str1, str2

!------------end of declaration------------------------------------------------

!open net-cdf file with read-only access
ncStatus = nf90_open (fileName, NF90_NOWRITE, ncId)
IF (ncStatus /= nf90_noerr) THEN
  CALL Catch ('error', 'GridLib',        &
  TRIM (nf90_strerror (ncStatus) )//': ',  &
  code = ncIOError, argument = fileName )
ENDIF

!retrieve time unit
CALL ParseTime (ncId, ref_time, time_unit)

!inquire dataset to retrieve number of dimensions, variables 
!and global attributes
ncStatus = nf90_inquire(ncId, nDimensions = nDims, &
                        nVariables = nVars,        &
                        nAttributes = nAtts        )
                  
CALL ncErrorHandler (ncStatus)

!search for time variable
DO i = 1, nVars
  attribute = ''
  ncStatus = nf90_get_att (ncId, varid = i, name = 'standard_name', &
                           values = attribute)
  
  IF (ncStatus == nf90_noerr) THEN !standard_name is defined
    IF ( attribute(1:4) == 'time' ) THEN
      idTime = i 
      EXIT   
    END IF
  ELSE !standard_name is not defined: search for variable named 'time'
     !ncStatus = nf90_inq_varid (ncId, 'time', varid = i )
     ncstatus = nf90_inquire_variable(ncId, varId = i, name = variableName)
     IF (LEN_TRIM(variableName) == 4 .AND. &
         variableName(1:4) == 'time' .OR. &
         LEN_TRIM(variableName) == 5 .AND. &
         variableName(1:5) == 'Times' ) THEN !variable 'time' found
       idTime = i 
       EXIT 
     END IF
  END IF
END DO

!retrieve time length
length = GetTimeSteps (ncId)

!compute dt
IF (DateTimeIsDefault(ref_time)) THEN
    slice2(1) = 1
    slice2(2) = 1
    ncStatus = nf90_get_var (ncId, idTime, str , start = slice2)
    CALL ncErrorHandler (ncStatus)
    !build datetime string from format used in netcdf file i.e 2007-10-11_00:00:00
    timeString = str(1:10) // 'T' // str(12:19) // '+00:00'
    date1 = timeString

    slice2(1) = 1
    slice2(2) = 2
    ncStatus = nf90_get_var (ncId, idTime, str , start = slice2)
    CALL ncErrorHandler (ncStatus)
    !build datetime string from format used in netcdf file i.e 2007-10-11_00:00:00
    timeString = str(1:10) // 'T' // str(12:19) // '+00:00'
    date2 = timeString

    dt = date2 - date1
ELSE
    slice(1) = 1
    ncStatus = nf90_get_var (ncId, idTime, time1 , start = slice)
    CALL ncErrorHandler (ncStatus)
 
    slice(1) = 2
    ncStatus = nf90_get_var (ncId, idTime, time2 , start = slice)
    CALL ncErrorHandler (ncStatus)

    dt = time2 - time1
    !convert in seconds
      SELECT CASE (time_unit)
        CASE ('minutes')
          dt = dt * minute
        CASE ('hours')
          dt = dt * hour
        CASE ('days')
          dt = dt * day
        CASE ('months')
          dt = dt * month
      END SELECT

END IF

!Check if dt is regular
IF (PRESENT (checkRegular) ) THEN
  IF (checkRegular) THEN
    DO i = 1, length - 1
         IF (DateTimeIsDefault(ref_time)) THEN
         
            slice2(1) = 1
            slice2(2) = i
            ncStatus = nf90_get_var (ncId, idTime, str1 , start = slice2)
            CALL ncErrorHandler (ncStatus)
      
            slice2(2) = i + 1
            ncStatus = nf90_get_var (ncId, idTime, str2 , start = slice2)
            CALL ncErrorHandler (ncStatus)
      
            timeString = str1(1:10) // 'T' // str1(12:19) // '+00:00'
            date1 = timeString
  
            timeString = str2(1:10) // 'T' // str2(12:19) // '+00:00'
            date2 = timeString
            timeSpan = date2 - date1     
         ELSE
            slice(1) = i
            ncStatus = nf90_get_var (ncId, idTime, time1 , start = slice)
            CALL ncErrorHandler (ncStatus)
      
            slice(1) = i + 1
            ncStatus = nf90_get_var (ncId, idTime, time2 , start = slice)
            CALL ncErrorHandler (ncStatus)
      
            IF (DateTimeIsDefault(ref_time)) THEN
                timeString = ToString (time1)
                timeString = timeString (1:4) // '-' // &
                             timeString (5:6) // '-' // &
                             timeString (7:8) // 'T' // &
                             timeString (9:10) // ':00:00+00:00'
                date1 = timeString
          
                timeString = ToString (time2)
                timeString = timeString (1:4) // '-' // &
                           timeString (5:6) // '-' // &
                           timeString (7:8) // 'T' // &
                           timeString (9:10) // ':00:00+00:00'
                date2 = timeString
          
                timeSpan = date2 - date1
          
            ELSE
                timeSpan = time2 - time1
                !convert in seconds
                SELECT CASE (time_unit)
                  CASE ('minutes')
                    timeSpan = timeSpan * minute
                  CASE ('hours')
                    timeSpan = timeSpan * hour
                  CASE ('days')
                    timeSpan = timeSpan * day
                  CASE ('months')
                    timeSpan = timeSpan * month
                END SELECT
            END IF
         END IF
       
         IF (timeSpan /= dt ) THEN
            CALL Catch ('error', 'GridLib',        &
                'time not regular in multidimensional grid')
         END IF
    
        END DO

  END IF
END IF


END FUNCTION GetDtGrid